home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Power Programmierung
/
Power-Programmierung (Tewi)(1994).iso
/
assemblr
/
library
/
sampler0
/
printer.asm
< prev
next >
Wrap
Assembly Source File
|
1986-03-01
|
26KB
|
515 lines
TITLE Printer
PAGE 66,132
;* * * * * * * * * * * * * * P R I N T E R * * * * * * * * * * * * * * *
;
; John C. Petrey
; (c) 1983
;
;
;
;
CSEG segment para public 'CODE'
org 100h
;
;
PRINTER proc far
assume cs:cseg,ds:cseg,es:nothing
;
jmp set_up
;
;Data Area
;
disk db 00h ;current default disk drive
bytes_left db 00h ;bytes of code left to read
sav_row db 02h ;start cursor at line 2
kbd_input db ' ' ;save keyboard input
print_lit db 'N' ;flag to indicate if we were printing literal
option_nbr db '0' ;option number printed on the screen
fcb db 00h ;1st byte of FCB (00h = default drive)
fcb2 db 'printer ' ;file name in FCB
fcb3 db 'dat' ;file extension in FCB
fcb4 db 25 dup(00h) ;remainder of FCB
dta db 128 dup('d') ;disk transfer area
eof db '$' ;end of disk transfer area
codes db 20 dup('c') ;user codes
line1 db 'Printer (1.1) - Special Print Functions$'
more db 'Change another setting? $'
nomatch db 'Please choose an option listed above $'
quest db 'Your Choice $'
option db 'Option $'
done db ' done!$'
escape db 'Esc - Exit$'
dash db ' - $'
no_file db 'PRINTER.DAT file not found or error in file$'
;
;Setup stuff
set_up:
push ds ;Set return segment address and ...
sub ax,ax ;put zero on stack ...
push ax ;so a RET returns us to starting address.
push cs ;Move work address into Data Segment ...
pop ds ;because this is a COM file.
;
;Save registers ;By saving register contents at program
push ax ;entry we insure exit will correctly
push bx ;return to DOS.
push cx
push dx
sti ;enable interrupts
;
;Set screen mode
mov al,2 ;80 x 25 B&W alpha
mov ah,0 ;BIOS interrupt 10 - set video mode
int 10h ;call BIOS to do it
;
;Clear screen
mov ah,6 ;clear screen with scroll active page up
mov al,0 ;entire window
mov cx,0 ;ch,cl = row,column of upper left corner
mov dh,24 ;dh = row to scroll to
mov dl,79 ;dl = column to scroll to
mov bh,7 ;attribute to be used on blank line
int 10h ;Call BIOS to scroll
;
;Title
mov dx,offset line1 ;get address of program title
call print ;print it on the screen
;
;Save current default disk drive
mov ah,19h ;DOS function to get default drive
int 21h ;Call DOS to do it - returned in AL
mov disk,al ;Save default disk returned in AL
;
;Get drive on which PRINTER.DAT file is located
mov si,80h ;point to command tail address
mov dh,[si] ;get length of command tail
tail:
cmp dh,00h ;Is their a command tail? or any bytes of tail left?
je set_dta ; no, go set DTA
dec dh ; yes, update bytes of tail left
inc si ; point to next byte in command tail
mov dl,[si] ; get contents of command tail
cmp dl,097 ;Is drive spec upper case?
jb upper ; yes, now go fold to a value
sub dl,32 ; no, fold down to upper case
upper:
sub dl,65 ;fold to a value
;
;Select disk drive
cmp dl,5 ;if value not valid (a - f) ...
ja tail ; get next command tail byte
cmp dl,0 ;if value not valid ...
jb tail ; get next command tail byte
mov ah,0Eh ;DOS function to select disk
int 21h ;call DOS to do it
;
;Set Disk Transfer Address
set_dta:
mov dx,offset dta ;get address of Disk Transfer Area (DTA)
mov ah,1Ah ;DOS function to set Disk Transfer Area (DTA)
int 21h ;call DOS to set DTA
;Open File Control Block
mov dx,offset fcb ;point to address of File Control Block (FCB)
mov ah,0fh ;DOS function to open file control block
int 21h ;call DOS to open file control block
mov bp,00h ;initialize base pointer - used later
;as offset into user codes
;
;Sequential read
read:
mov dx,offset fcb ;get address of file control block
mov ah,14h ;DOS function to read a record
int 21h ;call DOS to do it. AL returns 00 if successful.
cmp al,00h ;Was read successful?
je success ; Yes, continue with program
cmp al,03 ;Was partial record read?
je success ; Yes, continue with program
file_not_found:
mov dx,offset no_file ; No, get address of error message
call cursor ; print error message
jmp exit ; exit
success:
;
mov SI,00h ;initialize SI to zero - will use SI as offset
;within DTA (byte were currently working with)
;
cmp dta[si],'&' ;Is this the end of the users file?
jne not_end ; No, still more to read
jmp cont ; Yes, we're done reading users file
not_end: ;
;
cmp bytes_left,0 ;Were we reading codes when we reached end of DTA?
je not_reading ; No
jmp read_code ; Yes, go finsih reading codes
not_reading:
;
cmp dta[si],'$' ;Did we just finish printing a literal when we
;reached the end of the DTA?
je end_of_literal ; Yes, now read codes
;
cmp print_lit,'Y' ;Were we printing the literal when we reached the end of the DTA?
je finish_print ; Yes, go finish printing the literal
;
;Parse DTA - Print user literals & save user codes in opt0 - opt9
;
; User's file must be in the following format:
; 1) Literal of unspecified lengthed ending with "$"
; followed by exactly 2 control codes of which
; each must be 3 digits in decimal notation.
;
; 2) Last digit of last code in file should be followed
; by an ampersand "&"
;
; Reister uses:
; SI = on entry is address of start of DTA, subsequently
; it is the offset into the DTA (points to byte we
; are currently looking at.
; BP = offset within CODES
;
;
print_literal:
inc sav_row ;will print literal on next row down
mov dh,sav_row ;set new cursor position
call loc ;call locate cursor procedure to do it
mov dl,option_nbr ;get number of option (0 to 9)
mov ah,2 ;DOS function to print character in DL
int 21h ;let DOS print option number
inc option_nbr ;increment option nbr for next time
;
mov dx,offset dash ;get address of dash literal
call print ;print dash literal
;
finish_print:
mov dx,offset dta ;get address of start of DTA
add dx,si ;add SI to DX to get address of literal
;
mov di,dx ;set DI to address of literal
cmp byte ptr [di],0Dh ;Are we looking at a carriage return?
jne not_CR ; No, look at next byte
inc dx ; Yes, point to next byte
not_CR:
mov di,dx
cmp byte ptr [di],0Ah ;Are we looking at a Line Feed?
jne not_LF ; No, we can now print the literal
inc dx ; Yes, point to next byte
not_LF:
;
mov print_lit,'Y' ;Set flag to indicate we were printing literal
mov ah,9 ;DOS function to print literal pointed to in DX
int 21h ;call DOS to print literal
;
next_byte: ;This loop updates DX to point
;to the location in the DTA where
;the codes begin.
;
inc si ;Point to next byte in DTA.
;
cmp si,128d ;If we are at the end of the DTA,
jae read ;go get next sector of user's file.
;
cmp si,127d ;Are we at next to last byte in the DTA?
jne not_127 ; No, continue
cmp dta[si],'$' ; Yes, and is this a end of literal mark?
jne not_127 ; No, continue
mov bytes_left,6 ; Yes, will read 6 bytes of code
mov print_lit,'N' ; turn off printing literal flag
jmp read ; and get next sector
not_127:
;
cmp dta[si],'$' ;If DX pointing to end of literal,
je end_of_literal ;go read the codes following the literal.
;
jmp next_byte ;Otherwise, get next byte in DTA.
;
;
end_of_literal:
mov print_lit,'N' ;Set flag to indicate we are not printing the literal
mov bytes_left,6 ;Will read 6 bytes of code.
inc si ;Point to first byte of code.
cmp si,128d ;Are we are pointing to end of the DTA?
jbe first_byte ; No, read first byte of code.
jmp read ; Yes, go read next sector of users code.
;
read_code:
cmp bytes_left,6 ;If we reached the end of the DTA
je first_byte ;reading the codes this jump table
cmp bytes_left,5 ;will return us to the place where
je five_left ;we left off. The value in CL is
cmp bytes_left,4 ;the number of bytes we have left
je four_left ;to read.
cmp bytes_left,3
je three_left
cmp bytes_left,2
je two_left
cmp bytes_left,1
je last_byte_jmp ;This jump arround stuff is required only
jmp exit ;becasue it's to far for a conditional jump
last_byte_jmp: jmp last_byte
;
first_byte:
call byte1
mov dl,100d ;1st byte of code is 100's place
mov bl,0 ;initialize sum to zero - will use BL to
;accumulate hex value of users code
call byte2
cmp si,128 ;Are we at end of DTA?
jb five_left ; No, continue.
jmp read ; Yes, get next sector
;
five_left:
call byte1
mov dl,10d ;2nd byte of user's code is 10's place
call byte2
cmp si,128 ;Are we at end of DTA?
jb four_left ; No, continue.
jmp read ; Yes, get next sector.
;
four_left:
call byte1
add bl,al ;add one's place to sum in BL
call byte3
cmp si,128 ;Are we at end of DTA?
jb three_left ;No, continue.
jmp read ;Yes, get next sector.
;
three_left:
call byte1
mov dl,100d ;1st byte is 100's place
mov bl,0 ;initialize sum to zero - will use BL to
;accumulate hex value of users code
call byte2
cmp si,128 ;Are we at end of DTA?
jb two_left ; No, continue.
jmp read ; Yes, get next sector
;
two_left:
call byte1
mov dl,10d ;2nd byte is 10's place
call byte2
cmp si,128 ;Are we at end of DTA?
jb last_byte ; No, continue.
jmp read ; Yes, get next sector.
;
last_byte:
call byte1
add bl,al ;add one's place to sum in BL
call byte3
cmp si,128 ;Are we at end of DTA?
jb end_codes ; No, continue.
jmp read ; Yes, get next sector.
;
end_codes:
cmp dta[si],'&' ;Is next byte and end of file marker?
je cont ; Yes, we're done.
cmp bp,20d ;Have we written all 10 codes (20 bytes)
je cont ; Yes, we're done.
jmp print_literal ; No, print the next literal
;
;
cont:
inc sav_row ;set cursor to next row
mov dh,sav_row ;set new cursor position
call loc ;call locate procedure to set cursor at next row
mov dx,offset escape ;get address of "ESC - Exit" literal
call print ;print escape literal
;
mov sav_row,10h ;set cursor to be at line 16 (message line)
call msgs ;locate cursor at messages line
mov dx,offset quest ;print question "your choise"
call print
;
;
kboard: call kbd
mov [kbd_input],al ;save user's input in kbd_input
cmp al,1Bh ;Check to see if input was escape key
je escp ; Yes, go print message & exit
;
cmp al,'0' ;Check to see if input was less than zero
jl none ; Yes, print error message
;
cmp al,option_nbr ;Check to see if input was greater than nbr options
jae none ; Yes, print error message
;
sub al,30h ;fold user's ASCII character to a quantity
mov dl,2 ;get offset into codes by multiplying users
mul dl ;input in AL times 2 (2 bytes per option)
mov di,ax ;move result to DI (offset into CODES pointing
;to option user wants to execute ;
;
;First byte of code
mov dl,offset codes[di] ;get users code into DL
cmp dl,0 ;Is code zero?
je next_code ; Yes, get next code
;
call sendit ;send code in DL to printer
;
inc di ;point to next code
;
;Second byte of code
next_code:
mov dl,offset codes[di] ;get users code into DL
cmp dl,0 ;Is code zero?
je finished ; Yes, we're done - go print Done!
;
call sendit ;send code in DL to printer
;
finished:
mov dx,offset option ;get address of Option literal
call cursor ;call procedure to print literal
mov dl,[kbd_input] ;move user's keyboard input to DL
mov ah,2 ;DOS function to print character in DL
int 21h ;call DOS to print users keyboard input
mov dx,offset done ;get address of done! literal
call print ;call print procedure to print the literal
jmp again ;go ask user if he wants to play again
;
none:
call msgs ;clear the message line
mov dx,offset nomatch ;get address of nomatch literal
call print ;call print procedure to print literal
jmp kboard ;go wait for user input
;
escp:
call msgs ;blank-out message line
mov dh,23 ;position cursor at ...
call loc ;line 23
jmp exit ;We're DONE!!!!
;
again: call msgs ;blank-out message line line
mov dx,offset more ;print more literal
call print ;call print procedure to print more literal
jmp kboard ;go wait for user input
;
exit:
mov dl,disk ;get original default disk drive
mov ah,0Eh ;DOS function to set default disk drive
int 21h ;Call DOS to do it
;
pop dx ;restore registers so the
pop cx ;exit to DOS works OK.
pop bx
pop ax
int 20h ;Program terminate & return to DOS
;
PRINTER endp
;
;
;
BYTE1 proc
;
mov al,dta[si] ;get 1st byte of user's code
sub al,30h ;convert to hex quantity (from ASCII)
ret
BYTE1 endp
;
;
BYTE2 proc
;
mul dl ;Multiply times value in AL - result in AX
add bl,al ;Add low byte of result to BL
inc si ;point to next code in DTA
dec bytes_left ;first byte is done
ret
BYTE2 endp
;
;
BYTE3 proc
;
mov codes[bp],bl ;put user's code (converted to hex quantity) into CODE
inc bp ;point to next byte in CODE
inc si ;point to next byte in DTA
dec bytes_left ;now there are three bytes left
ret
BYTE3 endp
;
;
KBD proc ;This proc reads input from the keyboard
;
mov ah,1 ; DOS function to read char from keyboard
int 21h ; call DOS to do it
ret
KBD endp
;
;
;
CURSOR proc ;This proc restores the cursor to
;the position last saved, moves the
;cursor to down one line and lastly
;saves the new cursor position
;
push dx ;save address of display message
;
mov dh,sav_row ;get row last saved
inc dh ;add one to row
cmp dh,22 ;test to see if row is at 22 yet
jb no ; no, continue
mov dh,21 ; yes, set row to 21
no:
mov sav_row,dh ;save current row
call loc ;set cursor at new location
pop dx ;restore address of display message
call print ;call print procedure to print message
ret ;return
CURSOR endp
;
;
;
PGE proc ;This proc gets the active display
mov ah,15 ;page returning it in bh
int 10H
ret
PGE endp
;
;
;
LOC proc ;This proc sets the cursor at the
;row number set in dh
;
call pge ;get active page number
mov dl,0 ;column 0
mov ah,2
int 10H
ret
LOC endp
;
;
;
PRINT proc ;This proc sends the data pointed
;to by register DX to the screen
;for display
;
mov ah,9
int 21h
ret
PRINT endp
;
;
SENDIT proc ;This proc sends the contents of
;register DL to the printer
;
mov ah,5
int 21H
ret
SENDIT endp
;
;
MSGS proc ;This proc locates the cursor at
;the message line (line 15)
;
mov dh,15 ;locate cursor at line 15
call loc ;call locate procedure
mov cx,75 ;75 times we will ...
mov dl,' ' ;print spaces
print_space:
mov ah,2 ;DOS function to print character in DL
int 21h ;call DOS to print the space
loop print_space ;If CX is not zero, jump to print_space
mov dh,15 ;locate cursor at line 15
call loc ;call locate procedure
ret
MSGS endp
;
CSEG ends
end PRINTERooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooooo